home *** CD-ROM | disk | FTP | other *** search
/ Tech Arsenal 1 / Tech Arsenal (Arsenal Computer).ISO / tek-04 / oberrep.zip / OBERON.TXT < prev    next >
Text File  |  1990-10-10  |  40KB  |  1,062 lines

  1. The Programming Language Oberon
  2. (Revised Report)
  3.  
  4. N.Wirth
  5.  
  6. Make it as simple as possible, but not simpler.
  7. A. Einstein
  8.  
  9. 1. Introduction
  10.  
  11. Oberon is a general-purpose programming language that evolved from
  12. Modula-2. Its principal new feature is the concept of type extension. It
  13. permits the construction of new data types on the basis of existing ones
  14. and to relate them.
  15.  
  16. This report is not intended as a programmer's tutorial. It is intentionally
  17. kept concise. Its function is to serve as a reference for programmers,
  18. implementors, and manual writers. What remains unsaid is mostly left so
  19. intentionally, either because it is derivable from stated rules of the
  20. language, or because it would require to commit the definition when a
  21. general commitment appears as unwise.
  22.  
  23. 2. Syntax
  24.  
  25. A language is an infinite set of sentences, namely the sentences well
  26. formed according to its syntax. In Oberon, these sentences are called
  27. compilation units. Each unit is a finite sequence of symbols from a finite
  28. vocabulary. The vocabulary of Oberon consists of identifiers, numbers,
  29. strings, operators, delimiters, and comments. They are called lexical
  30. symbols and are composed of sequences of characters. (Note the distinction
  31. between symbols and characters.)
  32.  
  33. To describe the syntax, an extended Backus-Naur Formalism called EBNF is
  34. used. Brackets [ and ] denote optionality of the enclosed sentential form,
  35. and braces { and } denote its repetition (possibly 0 times). Syntactic
  36. entities (non-terminal symbols) are denoted by English words expressing
  37. their intuitive meaning. Symbols of the language vocabulary (terminal
  38. symbols) are denoted by strings enclosed in quote marks or words written in
  39. capital letters, so-called reserved words. Syntactic rules (productions)
  40. are marked by a $ sign at the left margin of the line.
  41.  
  42. 3. Vocabulary and representation
  43.  
  44. The representation of symbols in terms of characters is defined using the
  45. ASCII set. Symbols are identifiers, numbers, strings, operators,
  46. delimiters, and comments. The following lexical rules must be observed.
  47. Blanks and line breaks must not occur within symbols (except in comments,
  48. and blanks in strings). They are ignored unless they are essential to
  49. separate two consecutive symbols. Capital and lower-case letters are
  50. considered as being distinct.
  51.  
  52. 1. Identifiers are sequences of letters and digits. The first character
  53. must be a letter.
  54.  
  55. $  ident  =  letter {letter | digit}.
  56.  
  57. Examples:
  58.  
  59. x   scan   Oberon   GetSymbol    firstLetter
  60.  
  61. 2. Numbers are (unsigned) integers or real numbers. Integers are sequences
  62. of digits and may be followed by a suffix letter. The type is the minimal
  63. type to which the number belongs (see 6.1.). If no suffix is specified, the
  64. representation is decimal. The suffix H indicates hexadecimal
  65. representation.
  66.  
  67. A real number always contains a decimal point. Optionally it may also
  68. contain a decimal scale factor. The letter E (or D) is pronounced as
  69. "times ten to the power of". A real number is of type REAL, unless it has a
  70. scale factor containing the letter D; in this case it is of type LONGREAL.
  71.  
  72. $  number  =  integer | real.
  73. $  integer  =  digit {digit} | digit {hexDigit} "H" .
  74. $  real  =  digit {digit} "." {digit} [ScaleFactor].
  75. $  ScaleFactor    =  ("E" | "D") ["+" | "-"] digit {digit}.
  76. $  hexDigit  =    digit | "A" | "B" | "C" | "D" | "E" | "F".
  77. $  digit  =  "0" | "1" | "2" | "3" | "4" | "5" | "6" | "7" | "8" | "9".
  78.  
  79. Examples:
  80.  
  81. 1987
  82. 100H  = 256
  83. 12.3
  84. 4.567E8  = 456700000
  85. 0.57712566D-6  = 0.00000057712566
  86.  
  87. 3. Character constants are either denoted by a single character enclosed in
  88. quote marks or by the ordinal number of the character in hexadecimal
  89. notation followed by the letter X.
  90.  
  91. $  CharConstant  = """ character """ | digit {hexDigit} "X".
  92.  
  93. 4. Strings are sequences of characters enclosed in quote marks ("). A
  94. string cannot contain a quote mark. The number of characters in a string is
  95. called the length of the string. Strings can be assigned to and compared
  96. with arrays of characters (see 9.1 and 8.2.4).
  97.  
  98. $  string  =  """ {character} """ .
  99.  
  100. Examples:
  101.  
  102. "OBERON"    "Don't worry!"
  103.  
  104. 5. Operators and delimiters are the special characters, character pairs, or
  105. reserved words listed below. These reserved words consist exclusively of
  106. capital letters and cannot be used in the role of identifiers.
  107.  
  108. +   :=    ARRAY    IS       TO
  109. -   ^    BEGIN    LOOP       TYPE
  110. *   =    CASE    MOD       UNTIL
  111. /   #    CONST    MODULE       VAR
  112. ~   <    DIV    NIL       WHILE
  113. &   >    DO    OF       WITH
  114. .   <=    ELSE    OR
  115. ,   >=    ELSIF    POINTER
  116. ;   ..    END    PROCEDURE
  117. |   :    EXIT    RECORD
  118. (   )   IF      REPEAT
  119. [   ]    IMPORT    RETURN
  120. {   }    IN    THEN
  121.  
  122.  
  123. 6. Comments may be inserted between any two symbols in a program. They are
  124. arbitrary character sequences opened by the bracket (* and closed by *).
  125. Comments do not affect the meaning of a program.
  126.  
  127. 4. Declarations and scope rules
  128.  
  129. Every identifier occurring in a program must be introduced by a
  130. declaration, unless it is a predefined identifier. Declarations also serve
  131. to specify certain permanent properties of an object, such as whether it is
  132. a constant, a type, a variable, or a procedure.
  133.  
  134. The identifier is then used to refer to the associated object. This is
  135. possible in those parts of a program only which are within the scope of the
  136. declaration. No identifier may denote more than one object within a given
  137. scope. The scope extends textually from the point of the declaration to the
  138. end of the block (procedure or module) to which the declaration belongs and
  139. hence to which the object is local. The scope rule has the following
  140. amendments:
  141.  
  142. 1. If a type T is defined as POINTER TO T1 (see 6.4), the identifier T1 can
  143. be declared textually following the declaration of T, but it must lie
  144. within the same scope.
  145.  
  146. 2. Field identifiers of a record declaration (see 6.3) are valid in field
  147. designators only.
  148.  
  149. In its declaration, an identifier in the global scope may be followed by an
  150. export mark (*) to indicate that it be exported from its declaring module.
  151. In this case, the identifier may be used in other modules, if they import
  152. the declaring module. The identifier is then prefixed by the identifier
  153. designating its module (see Ch. 11). The prefix and the identifier are
  154. separated by a period and together are called a qualified identifier.
  155.  
  156. $  qualident = [ident "."] ident.
  157. $  identdef = ident ["*"].
  158.  
  159. The following identifiers are predefined; their meaning is defined in the
  160. indicated sections:
  161.  
  162. ABS       (10.2)  LEN       (10.2)
  163. ASH       (10.2)  LONG      (10.2)
  164. BOOLEAN    (6.1)   LONGINT   (6.1)
  165. BYTE       (6.1)   LONGREAL  (6.1)
  166. CAP       (10.2)  MAX       (10.2)
  167. CHAR       (6.1)   MIN       (10.2)
  168. CHR       (10.2)  NEW       (6.4)
  169. DEC       (10.2)  ODD       (10.2)
  170. ENTIER       (10.2)  ORD       (10.2)
  171. EXCL       (10.2)  REAL      (6.1)
  172. FALSE       (6.1)   SET       (6.1)
  173. HALT       (10.2)  SHORT     (10.2)
  174. INC       (10.2)  SHORTINT  (6.1)
  175. INCL       (10.2)  TRUE      (6.1)
  176. INTEGER    (6.1)
  177.  
  178. 5. Constant declarations
  179.  
  180. A constant declaration associates an identifier with a constant value.
  181.  
  182. $  ConstantDeclaration    =  identdef "=" ConstExpression.
  183. $  ConstExpression  =  expression.
  184.  
  185. A constant expression can be evaluated by a mere textual scan without
  186. actually executing the program. Its operands are constants  (see Ch. 8).
  187. Examples of constant declarations are
  188.  
  189. N  =  100
  190. limit  =  2*N -1
  191. all  =    {0 .. WordSize-1}
  192.  
  193. 6. Type declarations
  194.  
  195. A data type determines the set of values which variables of that type may
  196. assume, and the operators that are applicable. A type declaration is used
  197. to associate an identifier with the type.  Such association may be with
  198. unstructured (basic) types, or it may be with structured types, in which
  199. case it defines the structure of variables of this type and, by
  200. implication, the operators that are applicable to the components. There are
  201. two different structures, namely arrays and records, with different
  202. component selectors.
  203.  
  204. $  TypeDeclaration  =  identdef "=" type.
  205. $  type  =  qualident | ArrayType | RecordType | PointerType | ProcedureType.
  206.  
  207. Examples:
  208.  
  209. Table  =  ARRAY N OF REAL
  210.  
  211. Tree  =  POINTER TO Node
  212.  
  213. Node  =  RECORD key: INTEGER;
  214.     left, right: Tree
  215.     END
  216.  
  217. CenterNode  =  RECORD (Node)
  218.        name: ARRAY 32 OF CHAR;
  219.        subnode: Tree
  220.     END
  221.  
  222. Function*  =  PROCEDURE (x: INTEGER): INTEGER
  223.  
  224. 6.1. Basic types
  225.  
  226. The following basic types are denoted by predeclared identifiers. The
  227. associated operators are defined in 8.2, and the predeclared function
  228. procedures in 10.2. The values of a given basic type are the following:
  229.  
  230. 1.  BOOLEAN  the truth values TRUE and FALSE.
  231. 2.  CHAR  the characters of the ASCII set  (0X ... 0FFX).
  232. 3.  SHORTINT  the integers between MIN(SHORTINT) and MAX(SHORTINT).
  233. 4.  INTEGER  the integers between MIN(INTEGER) and MAX(INTEGER).
  234. 5.  LONGINT  the integers between MIN(LONGINT) and MAX(LONGINT).
  235. 6.  REAL  real numbers between MIN(REAL) and MAX(REAL).
  236. 7.  LONGREAL  real numbers between MIN(LONGREAL) and MAX(LONGREAL).
  237. 8.  SET  the sets of integers between 0 and MAX(SET).
  238. 9.  BYTE  (see 9.1 and 10.1)
  239.  
  240. Types 3 to 5 are integer types, 6 and 7 are real types, and together they
  241. are called numeric types. They form a hierarchy; the larger type includes
  242. (the values of) the smaller type:
  243.  
  244. LONGREAL  J  REAL  J  LONGINT  J  INTEGER  J  SHORTINT
  245.  
  246. 6.2. Array types
  247.  
  248. An array is a structure consisting of a fixed number of elements which are
  249. all of the same type, called the element type. The number of elements of an
  250. array is called its length. The elements of the array are designated by
  251. indices, which are integers between 0 and the length minus 1.
  252.  
  253. $  ArrayType  =  ARRAY length {"," length} OF type.
  254. $  length  =  ConstExpression.
  255.  
  256. A declaration of the form
  257.  
  258. ARRAY N0, N1, ... , Nk OF T
  259.  
  260. is understood as an abbreviation of the declaration
  261.  
  262. ARRAY N0 OF
  263.   ARRAY N1 OF
  264.   ...
  265.     ARRAY Nk OF T
  266.  
  267. Examples of array types:
  268.  
  269. ARRAY N OF INTEGER
  270. ARRAY 10, 20 OF REAL
  271.  
  272. 6.3. Record types
  273.  
  274. A record type is a structure consisting of a fixed number of elements of
  275. possibly different types. The record type declaration specifies for each
  276. element, called field, its type and an identifier which denotes the field.
  277. The scope of these field identifiers is the record definition itself, but
  278. they are also visible within field designators (see 8.1) referring to
  279. elements of record variables.
  280.  
  281. $  RecordType  =  RECORD ["(" BaseType ")"] FieldListSequence END.
  282. $  BaseType  =    qualident.
  283. $  FieldListSequence  =  FieldList {";" FieldList}.
  284. $  FieldList  =  [IdentList ":" type].
  285. $  IdentList  =  identdef {"," identdef}.
  286.  
  287. If a record type is exported, field identifiers that are to be visible
  288. outside the declaring module must be marked. They are called public fields;
  289. unmarked fields are called private fields.
  290.  
  291. Record types are extensible, i.e. a record type can be defined as an
  292. extension of another record type. In the examples above, CenterNode
  293. (directly) extends Node, which is the (direct) base type of CenterNode.
  294. More specifically, CenterNode extends Node with the fields name and
  295. subnode.
  296.  
  297. Definition: A type T0 extends a type T, if it equals T, or if it directly
  298. extends an extension of T. Conversely, a type T is a base type of T0, if it
  299. equals T0, or if it is the direct base type of a base type of T0.
  300.  
  301. Examples of record types:
  302.  
  303. RECORD day, month, year: INTEGER
  304. END
  305.  
  306. RECORD
  307.     name, firstname: ARRAY 32 OF CHAR;
  308.     age: INTEGER;
  309.     salary: REAL
  310. END
  311.  
  312. 6.4. Pointer types
  313.  
  314. Variables of a pointer type P assume as values pointers to variables of
  315. some type T. The pointer type P is said to be bound to T, and T is the
  316. pointer base type of P. T must be a record or array type. Pointer types
  317. inherit the extension relation of their base types. If a type T0 is an
  318. extension of T and P0 is a pointer type bound to T0, then P0 is also an
  319. extension of P.
  320.  
  321. $  PointerType    =  POINTER TO type.
  322.  
  323. If p is a variable of type P = POINTER TO T, then a call of the predefined
  324. procedure NEW(p) has the following effect (see 10.2): A variable of type T
  325. is allocated in free storage, and a pointer to it is assigned to p. This
  326. pointer p is of type P; the referenced variable p^ is of type T. Failure of
  327. allocation results in p obtaining the value NIL. Any pointer variable may
  328. be assigned the value NIL, which points to no variable at all.
  329.  
  330. 6.5. Procedure types
  331.  
  332. Variables of a procedure type T have a procedure as value. If a procedure P
  333. is assigned to a procedure variable of type T, the (types of the) formal
  334. parameters of P must be the same as those indicated in the formal type list
  335. of T. The same holds for the result type in the case of a function
  336. procedure (see 10.1). P must not be declared local to another procedure,
  337. and neither can it be a predefined procedure.
  338.  
  339. $  ProcedureType = PROCEDURE [FormalParameters].
  340.  
  341. 7. Variable declarations
  342.  
  343. Variable declarations serve to introduce variables and associate them with
  344. identifiers that must be unique within the given scope. They also serve to
  345. associate  fixed data types with the variables.
  346.  
  347. $  VariableDeclaration    =  IdentList ":" type.
  348.  
  349. Variables whose identifiers appear in the same list are all of the same
  350. type. Examples of variable declarations (refer to examples in Ch. 6):
  351.  
  352. i, j, k:  INTEGER
  353. x, y:  REAL
  354. p, q:  BOOLEAN
  355. s:    SET
  356. f:    Function
  357. a:    ARRAY 100 OF REAL
  358. w:    ARRAY 16 OF
  359.      RECORD ch: CHAR;
  360.         count: INTEGER
  361.      END
  362. t:  Tree
  363.  
  364. 8. Expressions
  365.  
  366. Expressions are constructs denoting rules of computation whereby constants
  367. and current values of variables are combined to derive other values by the
  368. application of operators and function procedures. Expressions consist of
  369. operands and operators. Parentheses may be used to express specific
  370. associations of operators and operands.
  371.  
  372. 8.1. Operands
  373.  
  374. With the exception of sets and literal constants, i.e. numbers and
  375. character strings, operands are denoted by designators. A designator
  376. consists of an identifier referring to the constant, variable, or procedure
  377. to be designated. This identifier may possibly be qualified by module
  378. identifiers (see Ch. 4 and 11), and it may be followed by selectors, if the
  379. designated object is an element of a structure.
  380.  
  381. If A designates an array, then A[E] denotes that element of A whose index
  382. is the current value of the expression E. The type of E must be an integer
  383. type. A designator of the form    A[E1, E2, ... , En] stands  for A[E1][E2]
  384. ... [En]. If p designates a pointer variable, p^ denotes the variable which
  385. is referenced by p. If r designates a record, then r.f denotes the field f
  386. of r. If p designates a pointer, p.f denotes the field f of the record p^,
  387. i.e. the dot implies dereferencing and p.f stands for p^.f, and p[E]
  388. denotes the element of p^ with index E.
  389.  
  390. The typeguard v(T0) asserts that v is of type T0, i.e. it aborts program
  391. execution, if it is not of type T0. The guard is applicable, if
  392.  
  393. 1.  T0 is an extension of the declared type T of v, and if
  394.  
  395. 2.  v is a variable parameter of record type or v is a pointer. In the
  396. latter case, condition 1. applies to the pointer base types of T and T0
  397. rather than to T and T0 themselves.
  398.  
  399. $  designator  =  qualident {"." ident | "[" ExpList "]" | "(" qualident ")" | "^" }.
  400. $  ExpList  =  expression {"," expression}.
  401.  
  402. If the designated object is a variable, then the designator refers to the
  403. variable's current value. If the object is a procedure, a designator
  404. without parameter list refers to that procedure. If it is followed by a
  405. (possibly empty) parameter list, the designator implies an activation of
  406. the procedure and stands for the value resulting from its execution. The
  407. (types of the) actual parameters must correspond to the formal parameters
  408. as specified in the procedure's declaration (see Ch. 10).
  409.  
  410. Examples of designators (see examples in Ch. 7):
  411.  
  412. i               (INTEGER)
  413. a[i]               (REAL)
  414. w[3].ch            (CHAR)
  415. t.key               (INTEGER)
  416. t.left.right           (Tree)
  417. t(CenterNode).subnode  (Tree)
  418.  
  419. 8.2. Operators
  420.  
  421. The syntax of expressions distinguishes between four classes of operators
  422. with different precedences (binding strengths). The operator ~ has the
  423. highest precedence, followed by multiplication operators, addition
  424. operators, and relations. Operators of the same precedence associate from
  425. left to right. For example, x-y-z stands for (x-y)-z.
  426.  
  427. $  expression  =  SimpleExpression [relation SimpleExpression].
  428. $  relation  =    "=" | "#" | "<" | "<=" | ">" | ">=" | IN | IS.
  429. $  SimpleExpression  =    ["+"|"-"] term {AddOperator term}.
  430. $  AddOperator    =  "+" | "-" | OR .
  431. $  term  =  factor {MulOperator factor}.
  432. $  MulOperator    =  "*" | "/" | DIV | MOD | "&" .
  433. $  factor  =  number | CharConstant | string | NIL | set |
  434. $    designator [ActualParameters] | "(" expression ")" | "~" factor.
  435. $  set    =  "{" [element {"," element}] "}".
  436. $  element  =  expression [".." expression].
  437. $  ActualParameters  =    "(" [ExpList] ")" .
  438.  
  439. The available operators are listed in the following tables.  In some
  440. instances, several different operations are designated by the same operator
  441. symbol.  In these cases, the actual operation is identified by the type of
  442. the operands.
  443.  
  444. 8.2.1. Logical operators
  445.  
  446. symbol    result
  447.  
  448.   OR    logical disjunction
  449.   &   logical conjunction
  450.   ~   negation
  451.  
  452. These operators apply to BOOLEAN operands and yield a BOOLEAN result.
  453.  
  454. p OR q    stands for  "if p then TRUE, else q"
  455. p & q  stands for  "if p then q, else FALSE"
  456. ~ p  stands for  "not p"
  457.  
  458. 8.2.2. Arithmetic operators
  459.  
  460. symbol    result
  461.  
  462.   +    sum
  463.   -    difference
  464.   *    product
  465.   /  quotient
  466.  DIV   integer quotient
  467.  MOD   modulus
  468.  
  469. The operators +, -, *, and / apply to operands of numeric types.  The type
  470. of the result is that operand's type which includes the other operand's
  471. type, except for division (/), where the result is the real type which
  472. includes both operand types. When used as operators with a single operand,
  473. - denotes sign inversion and + denotes the identity operation.
  474.  
  475. The operators DIV and MOD apply to integer operands only. They are related
  476. by the following formulas defined for any x and y:
  477.  
  478. x  =  (x DIV y) * y  +  (x MOD y)
  479. 0 <= (x MOD y) < y    or    y < (x MOD y) <= 0
  480.  
  481. .
  482.  
  483. 8.2.3.    Set operators
  484.  
  485. symbol    result
  486.  
  487.   +   union
  488.   -   difference
  489.   *   intersection
  490.   /   symmetric set difference
  491.  
  492. The monadic minus sign denotes the complement of x, i.e. -x denotes the set
  493. of integers between 0 and MAX(SET) which are not elements of x.
  494.  
  495. x - y  =  x * (-y)
  496. x / y  =  (x-y) + (y-x)
  497.  
  498. 8.2.4. Relations
  499.  
  500. symbol    relation
  501.  
  502.   =    equal
  503.   #    unequal
  504.   <    less
  505.   <=   less or equal
  506.   >    greater
  507.   >=   greater or equal
  508.   IN   set membership
  509.   IS  type test
  510.  
  511. Relations are Boolean. The ordering relations <, <=, >, and >= apply to the
  512. numeric types, CHAR, and character arrays (strings). The relations = and #
  513. also apply to the type BOOLEAN and to set, pointer, and procedure types. x
  514. IN s  stands for "x is an element of s". x must be of an integer type, and
  515. s of type SET. v IS T stands for "v is of type T" and is called a type
  516. test. It is applicable, if
  517.  
  518. 1.  T is an extension of the declared type T0 of v, and if
  519.  
  520. 2.  v is a variable parameter of record type or v is a pointer. In the
  521. latter case, condition 1. applies to the pointer base types of T and T0
  522. rather than to T and T0 themselves.
  523.  
  524. Assuming, for instance, that T is an extension of T0 and that v is a
  525. designator declared of type T0, then the test "v IS T" determines whether
  526. the actually designated variable is (not only a T0, but also) a T.
  527.  
  528. Examples of expressions (refer to examples in Ch. 7):
  529.  
  530. 1987           (INTEGER)
  531. i DIV 3        (INTEGER)
  532. ~p OR q        (BOOLEAN)
  533. (i+j) * (i-j)      (INTEGER)
  534. s - {8, 9, 13}       (SET)
  535. i + x           (REAL)
  536. a[i+j] * a[i-j]    (REAL)
  537. (0<=i) & (i<100)   (BOOLEAN)
  538. t.key = 0       (BOOLEAN)
  539. k IN {i .. j-1}    (BOOLEAN)
  540. t IS CenterNode    (BOOLEAN)
  541.  
  542. 9. Statements
  543.  
  544. Statements denote actions. There are elementary and structured statements.
  545. Elementary statements are not composed of any parts that are themselves
  546. statements. They are the assignment, the procedure call, and the return and
  547. exit statements. Structured statements are composed of parts that are
  548. themselves statements. They are used to express sequencing and conditional,
  549. selective, and repetitive execution. A statement may also be empty, in
  550. which case it denotes no action.  The empty statement is included in order
  551. to relax punctuation rules in statement sequences.
  552.  
  553. $  statement  =  [assignment | ProcedureCall |
  554. $    IfStatement | CaseStatement | WhileStatement | RepeatStatement |
  555. $    LoopStatement | WithStatement | EXIT | RETURN [expression] ].
  556.  
  557. 9.1. Assignments
  558.  
  559. The assignment serves to replace the current value of a variable by a new
  560. value specified by an expression. The assignment operator is written as
  561. ":=" and pronounced as becomes.
  562.  
  563. $  assignment  =  designator ":=" expression.
  564.  
  565. The type of the expression must be included by the type of the variable, or
  566. it must extend the type of the variable. The following exceptions hold:
  567.  
  568. 1.  The constant NIL can be assigned to variables of any pointer type.
  569.  
  570. 2.  Strings can be assigned to any variable whose type is an array of
  571. characters, provided the length of the string is less than that of the
  572. array. If a string s of length n is assigned to an array a , the result is
  573. a[i] = si for i = 0 ... n-1, and a[n] = 0X.
  574.  
  575. 3.  Values of the types CHAR and SHORTINT can be assigned to variables of
  576. type BYTE.
  577.  
  578. Examples of assignments (see examples in Ch. 7):
  579.  
  580. i := 0
  581. p := i = j
  582. x := i + 1
  583. k := log2(i+j)
  584. F := log2
  585. s := {2, 3, 5, 7, 11, 13}
  586. a[i] := (x+y) * (x-y)
  587. t.key := i
  588. w[i+1].ch := "A"
  589.  
  590. 9.2. Procedure calls
  591.  
  592. A procedure call serves to activate a procedure. The procedure call may
  593. contain a list of actual parameters which are substituted in place of their
  594. corresponding formal parameters defined in the procedure declaration (see
  595. Ch. 10). The correspondence is established by the positions of the
  596. parameters in the lists of actual and formal parameters respectively. There
  597. exist two kinds of parameters: variable and value parameters.
  598.  
  599. In the case of variable parameters, the actual parameter must be a
  600. designator denoting a variable. If it designates an element of a structured
  601. variable, the selector is evaluated when the formal/actual parameter
  602. substitution takes place, i.e. before the execution of the procedure. If
  603. the parameter is a value parameter, the corresponding actual parameter must
  604. be an expression. This expression is evaluated prior to the procedure
  605. activation, and the resulting value is assigned to the formal parameter
  606. which now constitutes a local variable (see also 10.1.).
  607.  
  608. $  ProcedureCall  =  designator [ActualParameters].
  609.  
  610. Examples of procedure calls:
  611.  
  612. ReadInt(i)  (see Ch. 10)
  613. WriteInt(j*2+1, 6)
  614. INC(w[k].count)
  615.  
  616. 9.3. Statement sequences
  617.  
  618. Statement sequences denote the sequence of actions specified by the
  619. component statements which are separated by semicolons.
  620.  
  621. $  StatementSequence  =  statement {";" statement}.
  622.  
  623. 9.4. If statements
  624.  
  625. $  IfStatement    =  IF expression THEN StatementSequence
  626. $    {ELSIF expression THEN StatementSequence}
  627. $    [ELSE StatementSequence]
  628. $    END.
  629.  
  630. If statements specify the conditional execution of guarded statements. The
  631. Boolean expression preceding a statement is called its guard. The guards
  632. are evaluated in sequence of occurrence, until one evaluates to TRUE,
  633. whereafter its associated statement sequence is executed. If no guard is
  634. satisfied, the statement sequence following the symbol ELSE is executed, if
  635. there is one.
  636.  
  637. Example:
  638.  
  639. IF (ch >= "A") & (ch <= "Z") THEN ReadIdentifier
  640. ELSIF (ch >= "0") & (ch <= "9") THEN ReadNumber
  641. ELSIF ch = 22X THEN ReadString
  642. ELSE SpecialCharacter
  643. END
  644.  
  645. 9.5. Case statements
  646.  
  647. Case statements specify the selection and execution of a statement sequence
  648. according to the value of an expression. First the case expression is
  649. evaluated, then the statement sequence is executed whose case label list
  650. contains the obtained value. The case expression and all labels must be of
  651. the same type, which must be an integer type or CHAR. Case labels are
  652. constants, and no value must occur more than once. If the value of the
  653. expression does not occur as a label of any case, the statement sequence
  654. following the symbol ELSE is selected, if there is one. Otherwise it is
  655. considered as an error.
  656.  
  657. $  CaseStatement  =  CASE expression OF case {"|" case} [ELSE StatementSequence] END.
  658. $  case  =  [CaseLabelList ":" StatementSequence].
  659. $  CaseLabelList  =  CaseLabels {"," CaseLabels}.
  660. $  CaseLabels  =  ConstExpression [".." ConstExpression].
  661.  
  662. Example:
  663.  
  664. CASE ch OF
  665.      "A" .. "Z":  ReadIdentifier
  666.   | "0" .. "9":  ReadNumber
  667.   | 22X :  ReadString
  668. ELSE  SpecialCharacter
  669. END
  670.  
  671. 9.6. While statements
  672.  
  673. While statements specify repetition. If the Boolean expression (guard)
  674. yields TRUE, the statement sequence is executed. The expression evaluation
  675. and the statement execution are repeated as long as the Boolean expression
  676. yields TRUE.
  677.  
  678. $  WhileStatement  =  WHILE expression DO StatementSequence END.
  679.  
  680. Examples:
  681.  
  682. WHILE j > 0 DO
  683.     j := j DIV 2; i := i+1
  684. END
  685.  
  686. WHILE (t # NIL) & (t.key # i) DO
  687.     t := t.left
  688. END
  689.  
  690. 9.7. Repeat Statements
  691.  
  692. A repeat statement specifies the repeated execution of a statement sequence
  693. until a condition is satisfied. The statement sequence is executed at least
  694. once.
  695.  
  696. $  RepeatStatement  =    REPEAT StatementSequence UNTIL expression.
  697.  
  698. 9.8. Loop statements
  699.  
  700. A loop statement specifies the repeated execution of a statement sequence.
  701. It is terminated by the execution of any exit statement within that
  702. sequence (see 9.9).
  703.  
  704. $  LoopStatement  =  LOOP StatementSequence END.
  705.  
  706. Example:
  707.  
  708. LOOP
  709.    IF t1 = NIL THEN EXIT END ;
  710.    IF k < t1.key THEN t2 := t1.left; p := TRUE
  711.    ELSIF k > t1.key THEN t2 := t1.right; p := FALSE
  712.    ELSE EXIT
  713.    END ;
  714.    t1 := t2
  715. END
  716.  
  717. Although while and repeat statements can be expressed by loop statements
  718. containing a single exit statement, the use of while and repeat statements
  719. is recommended in the most frequently occurring situations, where
  720. termination depends on a single condition determined either at the
  721. beginning or the end of the repeated statement sequence. The loop statement
  722. is useful to express cases with several termination conditions and points.
  723.  
  724. 9.9. Return and exit statements
  725.  
  726. A return statement consists of the symbol RETURN, possibly followed by an
  727. expression. It indicates the termination of a procedure, and the expression
  728. specifies the result of a function procedure. Its type must be identical to
  729. the result type specified in the procedure heading (see Ch. 10).
  730.  
  731. Function procedures require the presence of a return statement indicating
  732. the result value. There may be several, although only one will be executed.
  733. In proper procedures, a return statement is implied by the end of the
  734. procedure body. An explicit return statement therefore appears as an
  735. additional (probably exceptional) termination point.
  736.  
  737. An exit statement consists of the symbol EXIT. It specifies termination of
  738. the enclosing loop statement and continuation with the statement following
  739. that loop statement. Exit statements are contextually, although not
  740. syntactically bound to the loop statement which contains them.
  741.  
  742. 9.10. With statements
  743.  
  744. If a pointer variable or a variable parameter with record structure is of a
  745. type T0, it may be designated in the heading of a with clause together with
  746. a type T that is an extension of T0. Then this variable is treated within
  747. the with statement as if it had been declared of type T. The with statement
  748. assumes a role similar to the type guard, extending the guard over an
  749. entire statement sequence. It may be regarded as a regional type guard.
  750.  
  751. $  WithStatement  =  WITH qualident ":" qualident DO StatementSequence END .
  752.  
  753. Example:
  754.  
  755. WITH t: CenterNode DO name := t.name; L := t.subnode END
  756.  
  757. 10. Procedure declarations
  758.  
  759. Procedure declarations consist of a procedure heading and a procedure body.
  760. The heading specifies the procedure identifier, the formal parameters, and
  761. the result type (if any). The body contains declarations and statements.
  762. The procedure identifier is repeated at the end of the procedure
  763. declaration.
  764.  
  765. There are two kinds of procedures, namely proper procedures and function
  766. procedures. The latter are activated by a function designator as a
  767. constituent of an expression, and yield a result that is an operand in the
  768. expression. Proper procedures are activated by a procedure call. The
  769. function procedure is distinguished in the declaration by indication of the
  770. type of its result following the parameter list. Its body must contain a
  771. RETURN statement which defines the result of the function procedure.
  772.  
  773. All constants, variables, types, and procedures declared within a procedure
  774. body are local to the procedure. The values of local variables are
  775. undefined upon entry to the procedure. Since procedures may be declared as
  776. local objects too, procedure declarations may be nested.
  777.  
  778. In addition to its formal parameters and locally declared objects, the
  779. objects declared in the environment of the procedure are also visible in
  780. the procedure (with the exception of those objects that have the same name
  781. as an object declared locally).
  782.  
  783. The use of the procedure identifier in a call within its declaration
  784. implies recursive activation of the procedure.
  785.  
  786. $  ProcedureDeclaration  =  ProcedureHeading ";" ProcedureBody ident.
  787. $  ProcedureHeading  =    PROCEDURE ["*"] identdef [FormalParameters].
  788. $  ProcedureBody  =  DeclarationSequence [BEGIN StatementSequence] END.
  789. $  ForwardDeclaration  =  PROCEDURE "^" identdef [FormalParameters].
  790. $  DeclarationSequence    =  {CONST {ConstantDeclaration ";"} |
  791. $      TYPE {TypeDeclaration ";"} | VAR {VariableDeclaration ";"}}
  792. $      {ProcedureDeclaration ";" | ForwardDeclaration ";"}.
  793.  
  794. A forward declaration serves to allow forward references to a procedure
  795. that appears later in the text in full. The actual declaration - which
  796. specifies the body - must indicate the same parameters and result type (if
  797. any) as the forward declaration, and it must be within the same scope. An
  798. asterisk following the symbol PROCEDURE is a hint to the compiler and
  799. specifies that the procedure is to be usable as parameter and assignable to
  800. variables of a compatible procedure type.
  801.  
  802. 10.1. Formal parameters
  803.  
  804. Formal parameters are identifiers which denote actual parameters specified
  805. in the procedure call. The correspondence between formal and actual
  806. parameters is established when the procedure is called. There are two kinds
  807. of parameters, namely value and variable parameters. The kind is indicated
  808. in the formal parameter list. Value parameters stand for local variables to
  809. which the result of the evaluation of the corresponding actual parameter is
  810. assigned as initial value. Variable parameters correspond to actual
  811. parameters that are variables, and they stand for these variables. Variable
  812. parameters are indicated by the symbol VAR, value parameters by the absence
  813. of the symbol VAR. A function procedure without parameters must have an
  814. empty parameter list.  It must be called by a function designator whose
  815. actual parameter list is empty too.
  816.  
  817. Formal parameters are local to the procedure, i.e. their scope is the
  818. program text which constitutes the procedure declaration.
  819.  
  820. $  FormalParameters  =    "(" [FPSection {";" FPSection}] ")" [":" qualident].
  821. $  FPSection  =  [VAR] ident  {"," ident} ":" FormalType.
  822. $  FormalType  =  {ARRAY OF} qualident.
  823.  
  824. The type of each formal parameter is specified in the parameter list.  For
  825. variable parameters, it must be identical to the corresponding actual
  826. parameter's type, except in the case of a record, where it must be a base
  827. type of the corresponding actual parameter's type. For value parameters,
  828. the rule of assignment holds (see 9.1). If the formal parameter's type is
  829. specified as
  830.  
  831. ARRAY OF T
  832.  
  833. the parameter is said to be an open array parameter, and the corresponding
  834. actual parameter may be any array with the element type T.
  835.  
  836. In the case of a parameter with formal type BYTE, the corresponding actual
  837. parameter may be of type CHAR or SHORTINT. If the formal type of a variable
  838. parameter is ARRAY OF BYTE, any actual parameter type is permitted.
  839.  
  840. If a formal parameter specifies a procedure type, then the corresponding
  841. actual parameter must be either a procedure declared at level 0 or a
  842. variable (or parameter) of that procedure type. It cannot be a predefined
  843. procedure. The result type of a procedure can be neither a record nor an
  844. array.
  845.  
  846. Examples of procedure declarations:
  847.  
  848. PROCEDURE ReadInt(VAR x: INTEGER);
  849.    VAR i : INTEGER; ch: CHAR;
  850. BEGIN i := 0; Read(ch);
  851.    WHILE ("0" <= ch) & (ch <= "9") DO
  852.        i := 10*i + (ORD(ch)-ORD("0")); Read(ch)
  853.    END ;
  854.    x := i
  855. END ReadInt
  856.  
  857. PROCEDURE WriteInt(x: INTEGER);  (* 0 <= x < 10^5 *)
  858.    VAR i: INTEGER;
  859.        buf: ARRAY 5 OF INTEGER;
  860. BEGIN i := 0;
  861.    REPEAT buf[i] := x MOD 10;  x := x DIV 10;  INC(i) UNTIL x = 0;
  862.    REPEAT DEC(i); Write(CHR(buf[i] + ORD("0"))) UNTIL i = 0
  863. END WriteInt
  864.  
  865. PROCEDURE log2(x: INTEGER): INTEGER;
  866.    VAR y: INTEGER;  (*assume x>0*)
  867. BEGIN y := 0;
  868.    WHILE x > 1 DO x := x DIV 2; INC(y) END ;
  869.    RETURN y
  870. END log2
  871.  
  872. 10.2. Predefined procedures
  873.  
  874. The following table lists the predefined procedures.  Some are generic
  875. procedures, i.e. they apply to several types of operands.  v stands for a
  876. variable, x and n for expressions, and T for a type.
  877.  
  878. Function procedures:
  879.  
  880. Name     Argument type         Result type  Function
  881.  
  882.  
  883. ABS(x)    numeric type        type of x   absolute value
  884.  
  885. ODD(x)    integer type        BOOLEAN     x MOD 2 = 1
  886.  
  887. CAP(x)    CHAR                CHAR        corresponding capital letter
  888.  
  889. ASH(x, n) x, n: integer type  LONGINT     x * 2n,  arithmetic shift
  890.  
  891. LEN(v, n) v: array            LONGINT     the length of v in dimension n
  892.       n: integer type
  893.  
  894. LEN(v)  is equivalent with  LEN(v, 0)
  895.  
  896. MAX(T)    T = basic type      T           maximum value of type T
  897.       T = SET          INTEGER      maximum element of sets
  898.  
  899. MIN(T)    T = basic type      T           minimum value of type T
  900.       T = SET          INTEGER      0
  901.  
  902. Type conversion procedures:
  903.  
  904. Name       Argument type      Result type Function
  905.  
  906.  
  907. ORD(x)     CHAR, BYTE         INTEGER     ordinal number of x
  908.  
  909. CHR(x)     integer type, BYTE CHAR        character with ordinal number x
  910.  
  911. SHORT(x)   LONGINT            INTEGER     identity
  912.        INTEGER          SHORTINT
  913.        LONGREAL          REAL  (truncation possible)
  914.  
  915. LONG(x)    SHORTINT           INTEGER     identity
  916.        INTEGER          LONGINT
  917.        REAL           LONGREAL
  918.  
  919. ENTIER(x)  real type          LONGINT     largest integer not greater than x
  920.  
  921. Note that  ENTIER(i/j)  =  i DIV j
  922.  
  923. Proper procedures:
  924.  
  925. Name       Argument types          Function
  926.  
  927. INC(v)     integer type                   v := v+1
  928. INC(v, x)  integer type                   v := v+x
  929.  
  930. DEC(v)     integer type                   v := v-1
  931. DEC(v, x)  integer type                   v := v-x
  932.  
  933. INCL(v, x) v: SET; x: integer type        v := v + {x}
  934.  
  935. EXCL(v, x) v: SET; x: integer type        v := v - {x}
  936.  
  937. COPY(x, v) x: character array, string     v := x
  938.        v: character array
  939.  
  940. NEW(v)     pointer type                   allocate v^
  941.  
  942. HALT(x)    integer constant               terminate program execution
  943.  
  944. The second parameter of INC and DEC may be omitted, in which case its
  945. default value is 1. In HALT(x), x is a parameter whose interpretation is
  946. left to the underlying system implementation.
  947.  
  948. 11. Modules
  949.  
  950. A module is a collection of declarations of constants, types, variables,
  951. and procedures, and a sequence of statements for the purpose of assigning
  952. initial values to the variables. A module typically constitutes a text that
  953. is compilable as a unit.
  954.  
  955. $  module  =  MODULE ident ";"  [ImportList] DeclarationSequence
  956. $      [BEGIN StatementSequence] END ident "." .
  957. $  ImportList  =  IMPORT import {"," import} ";" .
  958. $  import  =  identdef [":" ident].
  959.  
  960. The import list specifies the modules of which the module is a client. If
  961. an identifier x is exported from a module M, and if M is listed in a
  962. module's import list, then x is referred to as M.x. If the form "M : M1" is
  963. used in the import list, that object declared within M1 is referenced as
  964. M.x .
  965.  
  966. Identifiers that are to be visible in client modules, i.e. outside the
  967. declaring module, must be marked by an export mark in their declaration. If
  968. a type imported from a module M is used in the specification of an exported
  969. object, (e.g. in its type or in its heading, but not in a procedure body),
  970. then also M must be marked in the import list.
  971.  
  972. The statement sequence following the symbol BEGIN is executed when the
  973. module is added to a system (loaded). Individual (parameterless) procedures
  974. can thereafter be activated from the system, and these procedures serve as
  975. commands.
  976.  
  977. Example:
  978.  
  979. MODULE Out;
  980.   (*exported procedures:  Write, WriteInt, WriteLn*)
  981.   IMPORT Texts, Oberon;
  982.  
  983.   VAR W: Texts.Writer;
  984.  
  985.   PROCEDURE Write*(ch: CHAR);
  986.   BEGIN Texts.Write(W, ch)
  987.   END ;
  988.  
  989.   PROCEDURE WriteInt*(x, n: LONGINT);
  990.     VAR i: INTEGER; a: ARRAY 16 OF CHAR;
  991.   BEGIN i := 0;
  992.     IF x < 0 THEN Texts.Write(W, "-"); x := -x END ;
  993.     REPEAT a[i] := CHR(x MOD 10 + ORD("0")); x := x DIV 10; INC(i) UNTIL x = 0;
  994.     REPEAT Texts.Write(W, " "); DEC(n) UNTIL n <= i;
  995.     REPEAT DEC(i); Texts.Write(W, a[i]) UNTIL i = 0
  996.   END WriteInt;
  997.  
  998.   PROCEDURE WriteLn*;
  999.   BEGIN Texts.WriteLn(W); Texts.Append(Oberon.Log, W.buf)
  1000.   END WriteLn;
  1001.  
  1002. BEGIN Texts.OpenWriter(W)
  1003. END Out.
  1004.  
  1005. Appendix: The Module SYSTEM
  1006.  
  1007. The module SYSTEM contains certain procedures that are necessary to program
  1008. low-level operations referring directly to objects particular to a given
  1009. computer and/or implementation. These include for example facilities for
  1010. accessing devices that are controlled by the computer, and facilities to
  1011. break the data type compatibility rules otherwise imposed by the language
  1012. definition. It is recommended to restrict their use to specific modules
  1013. (called low-level modules). Such modules are inherently non-portable, but
  1014. easily recognized due to the identifier SYSTEM appearing in their import
  1015. lists. The following specifications hold for the ETH implementation for the
  1016. NS32000 processor.
  1017.  
  1018. The procedures contained in module SYSTEM are listed in the following
  1019. tables. They correspond to single instructions compiled as in-line code.
  1020. For details, the reader is referred to the processor manual. v stands for a
  1021. variable, x, y, a, and n for expressions, and T for a type.
  1022.  
  1023. Function procedures:
  1024.  
  1025. Name       Argument type      Result type   Function
  1026.  
  1027.  
  1028. ADR(v)     any                LONGINT       address of variable v
  1029.  
  1030. BIT(a, n)  a: LONGINT         BOOLEAN       Mem[a][n]
  1031.        n: integer type
  1032.  
  1033. CC(n)      integer constant   BOOLEAN       Condition  n  (0 <= n < 16)
  1034.  
  1035. LSH(x, n)  x, n: integer type LONGINT       logical shift
  1036.  
  1037. ROT(x, n)  x, n: integer type LONGINT       rotation
  1038.  
  1039. SIZE(T)    any type           integer type  number of bytes required by T
  1040.  
  1041. VAL(T, x)  T, x: any type     T             x interpreted as of type T
  1042.  
  1043. Proper procedures:
  1044.  
  1045. Name        Argument types           Function
  1046.  
  1047.  
  1048. GET(a, v)       a: LONGINT;                v := Mem[a]
  1049.         v: any basic type
  1050.  
  1051. PUT(a, x)       a: LONGINT;                Mem[a] := x
  1052.         x: any basic type
  1053.  
  1054. MOVE(v0, v1, n) v0, v1: any type;          assign first n bytes of v0 to v1
  1055.         n: integer type
  1056.  
  1057. NEW(v, n)       v: any pointer type        allocate storage block of n bytes
  1058.         n: integer type        assign its address to v
  1059.  
  1060. File: Oberon2.Report.Doc / NW 30.8.89
  1061.  
  1062.